home *** CD-ROM | disk | FTP | other *** search
-
- title INTERRUPT DRIVEN ASYNC FOR MSC
- page 75,132
-
- ; Mike Dumdei, 6 Holly Lane, Texarkana TX 75503
- ; Version: 5-13-87
-
- comment |======================================================================
- This is the main module for the async routines and provides the basic functions
- necessary to perform serial I/O -- open/close ports, send/receive, and the
- interrupt handlers. Async_open makes a call to the MicroSoft C library
- function '_malloc' and the close function calls '_free' to dynamically allocate
- memory for the rx/tx ring buffers, therefore you must either use the MSC
- library when linking or provide your own routines for these functions.
- ==============================================================================|
-
- include casmhdr.h
- defseg COMM_TEXT
- include async.h ;define segments, equates, & macros
-
- IMPORT_NEAR <__ck_port_arg, __convert_bpds, __set_bpds>
- ifdef FARCODE
- IMPORT_FAR <_malloc, _free>
- else
- IMPORT_NEAR <_malloc, _free>
- endif ;import external functions
-
-
- _DATA segment
-
- ifdef LITES
- include lites1.inc ;debug data if using onscreen RX/TX ind
- endif
-
- ;---- Table of pointers to com port data structures
- public __port_dta_tbl
- __port_dta_tbl dw ofDG com1_dta ;table used to point SI to appropriate
- dw ofDG com2_dta ;com port data structure
-
- ;---- Com data structures for each port, initialized variables in order are:
- ; the segment & offset of the int hdlr, the int vctr nmbr assoc with the
- ; COM port, and the mask to enable the IRQ on the int cntrlr chip
- com1_dta port_dta <,TXT,ofTXT int_hdlr1,0ch,0efh>
- com2_dta port_dta <,TXT,ofTXT int_hdlr2,0bh,0f7h>
-
- ;---- Interrupt handler vectors and pointer to interrupt loop routine
- intrpt_tbl dw ofTXT msr_intrpt
- dw ofTXT tx_intrpt
- dw ofTXT rx_intrpt
- dw ofTXT lsr_intrpt
- intrpt_lp_adr dw ofTXT intrpt_loop
-
- _DATA ends
-
-
- begseg COMM_TEXT
-
- ;******************************************************************************
- ; ASYNC_OPEN -- Opens a comm port for use. Returns R_OK if successful else
- ; returns error code.
- ;******************************************************************************
- ;------------------------------------------------------------------------------
- ; This first section of the routine checks the arguments passed to the call
- ; for validity and converts them to usable form, initializes the data struc-
- ; ture for that port, and allocates space for the transmit and receive buffers.
- ;------------------------------------------------------------------------------
- publicproc _async_open
- push bp
- mov bp,sp
- push si
- push di ;stack frame, save reg variables
- push es
- push ds
- pop es ;save old ES and set ES=DS == DGROUP
- ;---- Get port address and init if valid && not already in use
- call __ck_port_arg ;rtrns lots of info -- see proc header
- pushf ;save return status
- mov cx,ds ;save user DS
- mov ax,bios_dta
- mov ds,ax
- assume ds:bios_dta
- mov ax,[bx] ;get base address of req com port from bios_dta
- mov ds,cx ;back to our DS
- assume ds:DGROUP
- popf ;restore status of call to __ck_port_arg
- ifdef DBUG
- jnc nxt_test1
- jmp noporterr
- nxt_test1:
- jz nxt_test2
- jmp inuseerr
- else
- jc noporterr ;CY = port arg passed to async_open was bad
- jnz inuseerr ;NZ = port has already been opened
- endif
- nxt_test2:
- or ax,ax
- je noporterr ;no good if BIOS doesn't have base address
- mov COM_BASE,ax ;store port base address
- ;---- Translate baud-parity-databit-stopbit string to comm chip language
- mov bx,BPDS_ptr ;get pointer to b-p-d-s string
- call __convert_bpds ;call conversion routine
- or ax,ax
- jnz err_exit ;error if rtn code wasn't 0
- ;---- Get size of transmit and receive buffers and allocate memory for them
- mov ax,Tx_len ;get size request for transmit buffer
- cmp ax,MAXBUFSIZE
- ja arg_err
- cmp ax,MINTXBUFSIZ
- jb arg_err ;make sure within MIN/MAX limits
- mov TX_SIZE,ax
- mov TX_FREE,ax ;init port data variables
- mov ax,Rx_len ;get size request for receive buffer
- cmp ax,MAXBUFSIZE
- ja arg_err
- cmp ax,MINRXBUFSIZ
- jb arg_err ;make sure within MIN/MAX limits
- mov RX_SIZE,ax
- mov RX_FREE,ax ;init port data variables
- add ax,Tx_len ;AX = total bytes of mem to allocate
- push ax ;setup for call to C lib's 'malloc'
- call _malloc ;allocate the space and get a pointer to it
- add sp,2
- ifdef FARDATA
- mov cx,ax
- add cx,dx
- jcxz memory_err ;not enough mem if NULL ptr returned
- else
- or ax,ax ;not enough mem if NULL ptr returned
- jz memory_err
- mov dx,ds ;segment for data in 'near model' is dgroup
- endif
- mov RXTX_SEG,dx ;save segment addrs of rx/tx buffers
- ;---- Finish initialization of the port data structure
- mov TX_TOP,ax ;save ptr to start of transmit bufr
- mov TX_IN,ax
- mov TX_OUT,ax ;init transmit buffer to empty condition
- ifdef DBUG
- call dsp_TXIN
- call dsp_TXOUT
- endif
- add ax,Tx_len ;calc start of receive bufr
- mov RX_TOP,ax ;save ptr to start of receive bufr
- mov RX_IN,ax
- mov RX_OUT,ax ;init receive buffer to empty condition
- ifdef DBUG
- call dsp_RXIN
- call dsp_RXOUT
- endif
- add ax,Rx_len
- mov RX_BTM,ax ;save ptr to last byte of rx bufr + 1
- mov STATWRD1,0 ;init STAT1 & STAT2 to zero
- mov STATWRD2,0ff08h ;MSR_NMSK=no MSR flow cntl, TX_STAT=txbuf empty
- jmp s init_inthndlr
-
- ;---- Error exit routines
- noporterr:
- mov ax,R_NOPORT
- jmp s err_exit
- inuseerr:
- mov ax,R_PORTINUSE
- jmp s err_exit
- arg_err:
- mov ax,R_BADARG
- jmp s err_exit
- memory_err:
- mov ax,R_NOMEM
- err_exit:
- xor bx,bx
- mov COM_BASE,bx ;show port not in use
- jmp s opn_exit ;back to C caller
-
- ;----------------------------------------------------------------------------
- ; At this point all data to initialize the port has been determined and the
- ; port data structure has been initialized. The next portion of the routine
- ; initializes the hardware to the selected parameters and sets up and enables
- ; the communication interrupt handling routines.
- ;----------------------------------------------------------------------------
- ;---- Initialize the communications interrupt handler
- init_inthndlr:
- ;---- Get and save old interrupt vector
- mov al,VECTOR_NBR
- mov ah,35h
- int 21h ;get current interrupt vector
- mov OLDVCTR_SEG,es
- mov OLDVCTR_OFST,bx ;save for when port closed
- ;---- Save old value of IER, LSR, and disable 8250 intrpts via the IER
- mov dx,COM_BASE
- inc dx ;xF9)interrupt enable register
- in al,dx
- jmp s $+2
- mov OLD_IER,al ;save original value of IER
- xor al,al
- out dx,al ;disable all types 8250 intrpts temporarily
- jmp s $+2
- inc dx
- inc dx ;xFB) line control register
- in al,dx
- mov OLD_LCR,al ;save original value of line contrl register
- ;---- Set the new interrupt vector, baud rate, & parity, data, stop bits
- mov dx,NEWVCTR_OFST
- mov al,VECTOR_NBR
- push ds
- mov ds,NEWVCTR_SEG
- mov ah,25h
- int 21h ;set new interrupt vector
- pop ds
- call __set_bpds ;set the baud,parity,data,stop bits, DisIntrprt
- ;---- Clear any pending interrupts
- mov dx,COM_BASE
- add dx,5 ;xFD) line status register
- in al,dx ;clear brk or data error type intrpts
- jmp s $+2
- sub dx,5 ;xF8) rx holding register
- in al,dx ;read rx register to clr its int status
- jmp s $+2
- inc dx
- inc dx ;xFA) interrupt id register
- in al,dx ;clr tx holding register empty interrupt cond
- jmp s $+2
- add dx,4 ;xFE) modem status register
- in al,dx ;read MSR to clear chng in stat type intrpts
- mov MSR_VAL,al ;save value of MSR
- jmp s $+2
- ;---- Enable RX, LSR, MSR intrpts, save old 8259 mask, & old 8250 MCR value
- dec dx
- dec dx ;xFC) pointing to modem cntrl reg (MCR)
- in al,dx
- jmp s $+2
- mov OLD_MCR,al ;save orig value of modem control reg
- ifdef RTSFALSE
- mov al,00001001b ;modem contrl value if RTS is to init'd low
- else
- mov al,00001011b
- endif
- out dx,al ;enable 8250 com intrpts, set DTR & RTS high
- jmp s $+2
- sub dx,3 ;xF9) pointing to intrpt enable reg
- mov al,00001101b
- out dx,al ;enable MSR, LSR, & RX intrpts
- jmp s $+2
- in al,IMR_8259
- jmp s $+2
- mov ah,MSK_8259
- not ah
- and ah,al
- mov OLD_8259_MSK,ah ;save old 8259 mask for this IRQ #
- and al,MSK_8259
- out IMR_8259,al ;enable 8259 IRQx interrupt
- ;---- Finished with initialization
- sti ;ready to go
- xor ax,ax ;return R_OK
- opn_exit:
- pop es
- pop di
- pop si
- pop bp
- ret ;restore regs and exit with r_code
- _async_open endp
-
- ;*****************************************************************************
- ; ASYNC_CLOSE -- This routine closes an opened communications port. All data
- ; in tx and rx buffers is lost. Returns R_NOPORT if port nmbr was invalid or
- ; already not active. Returns R_OK if successful.
- ;*****************************************************************************
- publicproc _async_close
- push bp
- mov bp,sp
- push si ;setup stk frame and save register varible
- call __ck_port_arg ;check the port arg and load pointers
- jz async_clsexit ;return err of invld arg or port not open
- inc dx ;xF9) enable interrupt register
- mov al,OLD_IER
- cli
- out dx,al ;restore intrpt enable reg to original cond
- jmp s $+2
- inc dx
- inc dx ;xFB) line control register (LCR)
- mov al,OLD_LCR
- out dx,al ;restore LCR to orig value
- jmp s $+2
- inc dx ;xFC) modem control register
- mov al,OLD_MCR
- out dx,al ;restore org status of MCR
- jmp s $+2
- in al,IMR_8259
- jmp s $+2
- or al,OLD_8259_MSK
- out IMR_8259,al ;restore IRQx to original condition
- push ds
- mov al,VECTOR_NBR
- mov dx,OLDVCTR_OFST
- mov ds,OLDVCTR_SEG
- mov ah,25h
- int 21h ;restore old interrupt vector
- sti
- pop ds
- mov dx,RXTX_SEG ;seg value of ptr
- mov ax,TX_TOP ;offset of ptr returned by call to 'malloc'
- push dx
- push ax ;push both to take care of either mem model
- call _free
- add sp,4 ;free mem alloc for RX/TX buffers
- xor ax,ax ;return R_OK
- mov COM_BASE,ax ;show port inactive
- async_clsexit:
- pop si
- pop bp
- ret ;clean up and exit to C
- _async_close endp
-
- ;*****************************************************************************
- ; ASYNC_TX -- Gets character passed by C caller and puts it in the transmit
- ; buffer. Returns R_TXERR if no room in bufr or port argument was invalid.
- ; Returns number bytes left in buffer if tx was successful.
- ;*****************************************************************************
- publicproc _async_tx
- push bp
- mov bp,sp
- push si
- push es ;setup stack and save regs
- call __ck_port_arg ;ck port argument & load pointers
- mov ax,R_TXERR
- jz async_texit ;bad port if ZR
- cmp TX_FREE,0
- je async_texit ;no good if no place to put input char
- mov es,RXTX_SEG ;get seg of rx/tx bufrs
- cli
- mov bx,TX_IN ;get ptr to tx bufr input
- mov al,TxChar ;get char passed by function call
- mov es:[bx],al ;put it in the tx bufr
- inc bx
- cmp bx,TX_BTM ;ck if time to loop buffer
- je lp_txptr
- store_txin:
- mov TX_IN,bx ;store new 'tx chars in' pointer
- ifdef DBUG
- call dsp_TXIN
- endif
- dec TX_FREE ;one less byte available in bufr
- and TX_STAT,n B_TXEMPTY ;clr the nothing to txmt bit in TX_STAT
- jz start_tx ;start txmtr if not on & no flow cntrl actv
- get_txfree:
- mov ax,TX_FREE ;get number bytes left in bufr
- async_texit:
- sti
- pop es
- pop si
- pop bp
- ret ;back to C caller
- ;---- Following moved here so no jmps taken for most common case (faster)
- lp_txptr:
- mov bx,TX_TOP ;reset ptr to top of ring buffer
- jmp s store_txin ;back to main flow
- start_tx:
- call __tx_inton ;start transmitter
- jmp s get_txfree ;back to main flow
- _async_tx endp
-
- ;******************************************************************************
- ; ASYNC_RX -- Receive character routine (read a char from rx buffer). Returns
- ; STAT1 as high byte. Returns '\0' as char read if buffer was empty and sets
- ; bit 6 of the STAT1 byte high. Bits 0-4 of STAT1 only indicate an error has
- ; occurred - not that it occurred on the char just read. Also bits 0-4 error
- ; conditions stay set until async_reset is called.
- ; STAT1: 0=rx bufr ovrfl 1=char overrun 2=parity err 3=framing err
- ; 4=break intrpt 5=invalid port 6=rx bufr empty 7=no carrier
- ;******************************************************************************
- publicproc _async_rx
- push bp
- mov bp,sp
- push si
- push es ;C stack frame, save regs
- call __ck_port_arg ;ck Port argument and setup pointers
- mov ax,0010000000000000b ;set invalid port bit just in case
- jz async_rexit
- cli
- mov ax,RX_FREE
- sub ax,RX_SIZE
- je rxbuf_empty ;jump if nothing in rx buffer
- mov bx,RX_OUT ;ptr to next char to come out of rx bufr
- mov es,RXTX_SEG ;get seg of rx buffer
- xor cx,cx
- mov cl,es:[bx]
- inc bx ;get a char & incrmnt pointer
- cmp bx,RX_BTM ;time to close loop on rx bufr?
- je lp_rxptr ;loop rx pointer if at bottom
- store_rxptr:
- mov RX_OUT,bx ;store ptr to next char to get
- ifdef DBUG
- call dsp_RXOUT
- endif
- inc RX_FREE ;another byte available in rx bufr
- test STAT2,B_XSENT ;has an XOFF been sent? (NZ = yes)
- jnz ckxflow_ctl ;see if now time to send XON if XOFF was sent
- setstat:
- xor ah,ah ;not rxempty, not invalid port
- setstat2:
- or ah,STAT1 ;get STAT bits set by RX/MSR intrpt routines
- mov al,cl ;AL = char read
- async_rexit:
- sti
- pop es
- pop si
- pop bp
- ret ;back to C caller
- ;---- Following moved here so no jmps taken for most common case (faster)
- rxbuf_empty:
- mov cl,al ;else set char retrned = '\0',
- mov ah,B_RXEMPTY ;set bit showing bufr empty (AH == 40h),
- jmp s setstat2 ;and go get rest of status information
- lp_rxptr:
- mov bx,RX_TOP ;loop back to top of bufr if it is
- jmp s store_rxptr ;back to main flow
- ckxflow_ctl:
- cmp RX_FREE,XONCOUNT
- jna setstat ;jmp if rxbuf to full to send XON yet
- and STAT2,n B_XSENT ;clr bit that indicates XOFF sent active
- mov TXIMMEDCHAR,XONCHAR ;XON will be next char tx'd
- and TX_STAT,n B_TXEMPTY ;set bit saying something needs tx'd
- jnz setstat ;done if tx alrdy on or other flw halt is actv
- push cx ;save char gotten from rx buffer
- call __tx_inton ;start the transmitter
- pop cx
- jmp s setstat ;restore char and back to main flow
- _async_rx endp
-
- ;****************************************************************************
- ; INTERRUPT ROUTINES:
- ; This is the interrupt handling routine. It is called whenever the receive
- ; holding register for an active port has a character or when transmitting
- ; whenever the transmit hold register for a transmitting port is ready for
- ; another character. Also monitors MSR and LSR interrupts.
- ;****************************************************************************
- ;---- Entry point for interrupt (BX set to slct appropriate port_dta struc)
- int_hdlr2 proc far
- push bx ;entry if COM2 interrupted
- mov bx,ofDG __port_dta_tbl+2 ;BX = ptr to ptr to com2_dta
- jmp s setup_proc
- int_hdlr1 proc far
- push bx ;entry if COM1 interrupted
- mov bx,ofDG __port_dta_tbl ;BX = ptr to ptr to com1_dta
- ;---- Allow other intrpts, save regs, and init ptrs to DGROUP, port_dta struc,
- ; and rx/tx buffers
- setup_proc:
- sti
- push ax
- push cx
- push dx
- push si
- push ds
- push es ;save registers
- mov ax,DGROUP
- mov ds,ax ;point to our data area
- mov si,[bx] ;SI = ptr to appropriate port_dta for this prt
- mov es,RXTX_SEG ;get segment where rx/tx bufrs are located
- ;---- Main interrupt handling loop. The loop gets the value in the UART
- ; intrpt ID register and checks the 'intrpt pending bit'. If the bit
- ; indicates a condition needs servicing the address of the top of the loop
- ; is pushed onto the stack and then a jump is made to the appropriate serv-
- ; ice routine. When the final 'ret' is encountered in the service routine,
- ; control passes back to the top of this loop.
- intrpt_loop:
- mov dx,COM_BASE ;DX = COM_BASE (base port address)
- inc dx
- inc dx ;xFA) -- Interrupt ident reg
- in al,dx
- shr al,1 ;slide 'pendng bit' into CY & ID bits to 1 & 0
- jc exit_intrpt ;done if pending bit indic all intrps processed
- dec dx
- dec dx ;xF8) - back to base register
- push DG:intrpt_lp_adr ;this will be return addrs (top of this loop)
- and ax,0000000000000011b ;make sure only int status infor is in AX
- shl ax,1
- mov bx,ax
- jmp DG:intrpt_tbl[bx] ;jmp to the appropriate service routine
- ;---- Exit interrupt routine
- exit_intrpt:
- cli
- mov al,20h
- out ICR_8259,al ;send 'end of interrupt' to 8259
- pop es
- pop ds
- pop si
- pop dx
- pop cx
- pop ax
- pop bx ;restore registers
- iret ;exit interrupt
- int_hdlr1 endp
- int_hdlr2 endp
-
- ;---- Interrupt service routine line status register interrupt.
- localproc lsr_intrpt
- add dx,5 ;xFD) line status register
- in al,dx ;reading LSR clears interrupt cond
- and al,00011110b ;mask off desired bits
- or STAT1,al ;put them in STAT1
- ret ;back to interrupt loop
- lsr_intrpt endp
-
- ;---- Interrupt service routine for modem status register change. Used to
- ; keep CD bit in STAT1 updated and as part of CTS, DSR, & CD flow
- ; procedures.
- localproc msr_intrpt
- add dx,6 ;xFE) modem status register
- in al,dx ;reading MSR clears interrupt cond
- mov MSR_VAL,al ;store MSR
- mov ah,al ;save MSR reg in AH also
- mov bl,n B_CD
- and STAT1,bl ;clr NOT CD bit (!CD) in STAT1 byte
- not bl
- and ah,bl ;mask MSR val to isolate CD bit
- xor ah,bl ;invert CD to make it !CD
- or STAT1,ah ;update !CD in STAT1 byte
- mov bx,STATWRD2 ;BH=MSR monitor mask, BL=TX_STAT byte
- and bl,bh ;clr monitored bits in TX_STAT
- not bh
- and al,bh ;mask out un-monitored bits in MSR value
- xor al,bh ;change monitored bits to their NOT function
- or al,bl ;combine updtd monitr bits with TX_STAT
- mov TX_STAT,al ;save new TX_STAT
- jnz msr_exit ;NZ == tx int running, noth to tx, or flow halt
- jmp __tx_inton ;if none of abv is true, time to strt tx bak up
- msr_exit:
- ret ;back to intrpt loop
- msr_intrpt endp
-
- ;---- Interrupt service routine for a 'char received' interrupt. Received char
- ; is placed in RX bufr unless it is full. If the bufr is full, char is
- ; ignored and rx bufr ovrflw bit is set in STAT1. Also performs XON/XOFF
- ; protocol functions and high bit stripping when using those options.
- localproc rx_intrpt
- in al,dx ;get char from 8250 hold reg
- ifdef LITES
- call rxlites ;dsplay debug rx lite if using
- endif
- and al,STRIP_MASK ;do bit stripping according to strip mask val
- test STAT2,B_XUSE ;using XON/XOFF protocol?
- jnz ck_xchar ;jmp to ck for XON or XOFF if using protcl
- ck_rxfull:
- cmp RX_FREE,0 ;any room left?
- je rx_overflow
- store_char:
- mov bx,RX_IN
- mov es:[bx],al ;else store the received char
- inc bx ;advance bufr pointer
- cmp bx,RX_BTM ;is it time to make the circle?
- je lp_rxptri
- store_rxptri:
- mov RX_IN,bx ;save new RX_IN ptr
- ifdef DBUG
- call dsp_RXIN
- endif
- dec RX_FREE ;one less byte avlbl in bufr
- cmp RX_FREE,XOFFCOUNT ;bytes free lower than XOFF level?
- jb ckifneed_XOFFsnt
- ret ;done if plenty room in rx buffer
- ckifneed_XOFFsnt:
- mov al,STAT2 ;get STAT2 in AL - several cks on it
- and al,B_XUSE+B_XSENT ;using XON/OFF? / msk unwanted bits in STAT2
- jnz send_xoff_ck2
- ret ;done if not using XON/OFF prtcl
- send_xoff_ck2:
- and al,B_XSENT
- jz send_xoff1 ;ZR = XOFF not alrdy sent
- dec XTXRPT ;ck if XOFF has been ignored for 'x' # of chars
- jz send_xoff2 ;send another XOFF if its been ignored
- ret ;else back to intrpt loop
- send_xoff1:
- or STAT2,B_XSENT ;set bit showing XOFF sent
- send_xoff2:
- mov XTXRPT,REPTXOFFVAL ;set up 'ignored' counter
- mov TXIMMEDCHAR,XOFFCHAR ;XOFF will be next char tx'd
- and TX_STAT,n B_TXEMPTY ;clr bit that indicates nothing to txmt
- jz __tx_inton ;strt tx if not alrdy on or other flow hlt actv
- ret ;back to interrupt loop
- ;---- Following moved out of main line of rx intrpt routn in attempt to get
- ; fastest performance in most likely to occur cases.
- rx_overflow:
- or STAT1,B_RXOVF ;set bit for rx bufr ovfl if no room
- ret
- lp_rxptri:
- mov bx,RX_TOP
- jmp s store_rxptri
- ck_xchar:
- cmp al,XOFFCHAR
- je xoff_rcvd ;jmp if char was an XOFF
- test STAT3,B_XONANY
- jnz ck_xoffactv ;jmp if any char can be an XON
- cmp al,XONCHAR ;was it a real XON?
- jne ck_rxfull ;back to main rxintrpt stream if not XON
- xon_rcvd:
- and TX_STAT,n B_XRXD ;clr bit showing XOFF rx'd
- jz __tx_inton ;rstrt tx if something to tx, no othr flw hlt
- ret ;back to intrpt loop
- ck_xoffactv:
- test TX_STAT,B_XRXD
- jnz xon_rcvd ;clr XOFF if active and any char can be XON
- jmp s ck_rxfull ;else treat char as normal char
- xoff_rcvd:
- or TX_STAT,B_XRXD ;set bit showing XOFF rx'd (will shut dn tx)
- ret ;back to intrpt loop
- rx_intrpt endp
-
- ;---- This procedure is called to initiate tx interrupts. Falls
- ; into the tx interrupt handler.
- localproc __tx_inton
- public __tx_inton
- mov dx,COM_BASE
- add dx,5 ;xFD)line status register
- wttxempty:
- in al,dx
- and al,00100000b ;test if tx hold reg is empty
- jz wttxempty ;and wait for it to be empty if its not
- jmp s $+2
- sub dx,4 ;xF9)intrpt enable register
- in al,dx ;get UART interrupt mask
- jmp s $+2
- or al,00000010b ;set TX intrpts bit
- out dx,al ;send new mask to the 8250
- or TX_STAT,B_TXION ;set bit in TX_STAT that says tx intrpts on
- dec dx ;xF8) tx hold register
- __tx_inton endp
-
- ;---- Interrupt service routine for transmitter ready condition. This routine
- ; first checks to see if any flow control has been activated and shuts off
- ; tx interrupts if it has. Next it looks at the TXIMMEDCHAR and if it is
- ; not a null transmits it next otherwise transmits the next buffer char.
- localproc tx_intrpt
- mov al,FLOW_MASK
- and al,TX_STAT
- jnz __shutoff_tx ;shutoff tx'r if XOFF, !CTS, !DSR, or !CD actv
- xor al,al
- xchg al,TXIMMEDCHAR
- or al,al ;ck if TXIMMED was a null & clr it for nxt time
- jnz txi_char ;jmp if TXIMMED
- mov ax,TX_SIZE
- cmp ax,TX_FREE
- je nomore_tx ;jmp if nothing left to transmit
- mov bx,TX_OUT ;pointer to next buf char to transmit
- mov al,es:[bx] ;get tx buffer character
- inc TX_FREE ;updt tx free bufr space value
- inc bx
- cmp bx,TX_BTM
- jne updt_txptr
- mov bx,TX_TOP
- jmp s $+2
- updt_txptr:
- mov TX_OUT,bx ;update the tx buffer pointer
- ifdef DBUG
- call dsp_TXOUT
- endif
- txi_char:
- out dx,al ;send the character
- ifdef LITES
- call txlites
- endif
- ret ;else finished with tx routine
- nomore_tx:
- or TX_STAT,B_TXEMPTY ;set bit showing nothing to tx
- localproc __shutoff_tx
- public __shutoff_tx
- inc dx ;xF9) interrupt enable register
- in al,dx
- jmp s $+2
- and al,00001101b
- out dx,al ;mask tx interrupt bit off in 8250
- and TX_STAT,n B_TXION ;clr bit in TX_STAT that indic tx is on
- ret ;finished
- __shutoff_tx endp
- tx_intrpt endp
-
- ifdef DBUG
- include dbug.inc ;display ring bufr ptr values debug code
- endif
- ifdef LITES
- include lites2.inc ;onscreen rx/tx indicator code
- endif
-
- endseg COMM_TEXT
- end